Coding Rules for developments in BigDFT
This page should summarize some of the best practices which have been found to have successful developments. The idea of this page is that it should be regularly updated such that eventually all of the source lines of the code are compliant with it. At least the new developments in the code should try to fit as possible to the specifications in this page.
Here follows some ideas collected during BigDFT experience.
Coding rules are often confused with beautification rules, such as defining formats of variables, indentation length, naming conventions and so on. In these pages such aspects are only partly considered. This is mainly due to the fact that a collaborative code have little chances to appear nice to newcomers, particularly when the sensibilities of collaborators are strongly different. The idea is that every of the rules described here has a reason, which is not necessarily explained.
Low level operations
In the BigDFT code, all the allocations and the I/O operations
should be intercepted by the flib
wrappers collections. Therefore,
direct allocations and direct writing are not permitted.
For the allocations, one should use the allocation procedures as suggested by the memory managment examples. And for the I/O, the yaml output. This is very important such as to preserve the modular structure of the code and to track performance bottlenecks as well as to handle tests and post-processing procedures.
Ideally, also the MPI
operations and the linear algebra should pass
through the BigDFT wrappers, but there are still in the sources a number
of points where this does not happen (yet… :)).
Subprograms writing
Let us start with the most common points:
implicit none
A routine or a function must have implicit none. this is fundamental in a complex code which is full of derived datatypes, rich of long source line that cannot be controlled for typos and so on. I hope this should be enough to you. Also, it is good practice to use the first letter of a variable to distinguish its (intrinsic) type, line in the old-fashioned implicit real*8 conventions. It might appear odd to define real variable starting with letters i or n or, conversely, integer variables starting with x.
Another important point is loop variables. In general, the index should recall the range of the loop, as in the example:
do iorb=1,norb
[...]
end do
dummy indices like i and ii should be used only when the loop is so small to be understood easily at a first look. Otherwise having the index is a good guide-to-the-eye.
Dummy arguments
The rules for writing dummy arguments of a routine often are a matter of taste. There is no preferential order in the dummy arguments (except of course the one imposed by Fortran norm, like optionals in the end), but there are some rules which are important for the variable declarations in a routine. After several years, the rationale found is the following. Some day, it could be scripted and tested. Here follow the rules in order of importance (nested each other of course):
Subroutines, function or procedures as arguments should go at the very end;
First non-optional, then optional arguments, like in the routine arguments;
First intent(in), then intent(inout), then intent(out) arguments. Pointer arguments without intent might be put either close to the corresponding intent (to guide the reader) or at the end.
First scalar variables, then arrays. Arrays should be declared in ascending rank order (though there is no actual reason for this latter rule);
the order for the types in the declaration should be the following (in order of kind):
Logicals;
Integers;
Reals;
Complex;
Derived types (in alphabetical order to make rules impossible ;))
Character variables (which are the closest to arrays).
These rules comes from the fact that a compiler wants the variable which are used in the declaration to be declared first. By following these rules the risk of non compilation is minimized.
Local arguments
The separation of local variables and arguments should be indicated with a commentary, like:
!local variables
The above mentioned priorities (when applicable of course) should also be used for the local variables. Rules two and three above should be replaced by
Parameters should be declared first in local variables declarations
These rules implies that no parameters should appear explicitly before the declaration of the local variables. In other terms, the dummy argument of a routine should not depend explicitly on parameters which are declared locally. This helps in avoiding nasty side-effects which might arise from bad declaration of such parameters in calling. Modules should be used when this is necessary. Also, all routines which are used as implicit interface should be declared as external.
Fortran Modules
Modules are useful tools in Fortran and they have to be used wisely (useless phrase). The main function of modules in BigDFT is to define the derived types and the main method associated with them. A good module should contain only the methods associated to the types which it defines which require explicit interfaces. This means, subprograms which are:
Functions (such as to avoid multiple declaration in local variables);
Declared as pure, recursive or elemental (compiler should know about them);
Contains pointers, allocatable arrays or assumed-shape arrays as dummy arguments (the descriptor has to be passed);
Contains optional arguments or arguments with the transfer attribute;
Contains dummy arguments which are procedure with explicit interfaces.
To this aim no module should be conceived with only aim of exporting interfaces of routines which are outside of it. This is to improve maintainability and reduce sources of errors. Of course, routines which do not need explicit interfaces may be contained into modules, if it is important to keep track of their arguments for example.
An important constraint that each module should implement is the overriding of the public attribute for the module subobjects. Therefore the statement
private
should be always present for any module which uses other modules. This is important because without this statement the module will also export the public routines of the used module. If a higer level routine uses both modules the compiler has a symbol duplication and resolving that might lead to compiler errors or long compilation times. In addition, it would clarify to the user which are the methods that each module exports. It is therefore recommended to relax this constraint only in very special cases like low-level modules or very high-level ones, which will be used exclusively.
Dangerous practices
The Fortran specification allows the usage of Fortran Modules in many ways. Most of the provided functionalities are useful and simplify developments, yet there are a few which are very dangerous and might contribute in creating programs which are prone to runtime errors and difficult to debug. These bad practices (in my opinion) have contributed in creating the wrong impression that module should be avoided as most as possible for having a robust Fortran code. Here we collect some of these practices:
Usage of modules to avoid declaration of local variables: this is (by far) the most dangerous practice, for mainly two reasons:
The code becomes difficult to read: the top-level routines use local variables which are defined in the module and have unclear type and rank. When debugging, this might become a real maintainance problem.
(Very important): Fortran specification does not guarantee the preservation of the status of public variables that does not have the
parameter
orsave
attribute (either explicitly or implicitly declared via initialization value). If these variables needs to be accessed from outside the module, you must declare them withsave
attribute. Bugs which might be created by this practice are increadibly nasty and difficult to find (as they might be non-reproductible). Indeed, the Fortran spec says (Metcalf, Reid, Cohen, Oxford Press, 2004): “On return from a subprogram that accesses a variable in a module, the variable becomes undefined unless the main program accesses the module, another subprogram in execution accesses the module, or the variable has the save attribute”
Declare public variables which are accessed and modified by routines which are outside the module: even if this seems a “innocent” practice, this complicates things when many developers are involved in a common project. The most recent Fortran 2003/08 specification provide the
protected
attribute of a variable exactly for this reason. It is always better to avoid public global variables of a module. Accessors (in form of subroutines or functions) might then be written to control the status of internal variables.
Derived types creators and destructors
The main functionality of modules which are (or should be) used in BigDFT are for derived type definitions and manipulations. Therefore it is important that each of the derived type defined in the modules comes with its methods to create and manipulate it. Let us consider for example a derived type, such as
!>Structure of the system. This derived type contains the information about the physical properties
type, public :: atomic_structure
character(len=1) :: geocode !< @copydoc poisson_solver::doc::geocode
character(len=5) :: inputfile_format !< Can be xyz ascii or yaml
character(len=20) :: units !< Can be angstroem or bohr
integer :: nat !< Number of atoms
integer :: ntypes !< Number of atomic species in the structure
real(gp), dimension(3) :: cell_dim !< Dimensions of the simulation domain (each one periodic or free according to geocode)
!pointers
real(gp), dimension(:,:), pointer :: rxyz !< Atomic positions (always in AU, units variable is considered for I/O only)
character(len=20), dimension(:), pointer :: atomnames !< Atomic species names
integer, dimension(:), pointer :: iatype !< Atomic species id
integer, dimension(:), pointer :: ifrztyp !< Freeze atoms while updating structure
integer, dimension(:), pointer :: input_polarization !< Used in AO generation for WFN input guess
type(symmetry_data) :: sym !< The symmetry operators
end type atomic_structure
(please note Doxygen documentation close to each variable). Such a derived type, when used as a local variable in a routine or in the main program, has a undefined status. Therefore methods have to be provided which constitute the basis to define each element of the structure. We call such methods the constructors, event if they do not make the derived type directly usable. There should always be two subprograms associated to these constructors, namely a routine and the corresponding function. Each of the ultimate component of the derived type should be initialized. Should one component be a derived type itself, the same method have to be used.
pure function atomic_structure_null() result(astruct)
implicit none
type(atomic_structure) :: astruct
call nullify_atomic_structure(astruct)
end function atomic_structure_null
pure subroutine nullify_atomic_structure(astruct)
implicit none
type(atomic_structure), intent(out) :: astruct
astruct%geocode='X'
astruct%inputfile_format=repeat(' ',len(astruct%inputfile_format))
astruct%units=repeat(' ',len(astruct%units))
astruct%nat=-1
astruct%ntypes=-1
astruct%cell_dim=0.0_gp
nullify(astruct%input_polarization)
nullify(astruct%ifrztyp)
nullify(astruct%atomnames)
nullify(astruct%iatype)
nullify(astruct%rxyz)
call nullify_symmetry_data(astruct%sym)
end subroutine nullify_atomic_structure
If all the ultimate component of a derived type are non-pointer intrinsic types, then only the function can be defined. Otherwise the subroutine have to be used such as to avoid explicit pointer association between pointer components of the derived type, which is forbidden for a pure function. The choice of declaring these function as pure is to enforce the concept that a constructor should not impose side-effects to the program. If these requirements are not possible, the developer should think on why it is so.
Another comment should be raised about automatic constructors. Fortran specification provides the facility of default initialization of a structure, for example by providing
!> Contains all energy terms
type, public :: energy_terms
real(gp) :: eh =0.0_gp !< Hartree energy
real(gp) :: exc =0.0_gp !< Exchange-correlation energy
real(gp) :: evxc =0.0_gp !< Energy from the exchange-correlation potential
real(gp) :: eion =0.0_gp !< Ion-Ion interaction
real(gp) :: edisp =0.0_gp !< Dispersion force
real(gp) :: ekin =0.0_gp !< Kinetic term
real(gp) :: epot =0.0_gp
real(gp) :: eproj =0.0_gp
real(gp) :: eexctX =0.0_gp
real(gp) :: ebs =0.0_gp
real(gp) :: eKS =0.0_gp
real(gp) :: trH =0.0_gp
real(gp) :: evsum =0.0_gp
real(gp) :: evsic =0.0_gp
real(gp) :: excrhoc =0.0_gp
real(gp) :: eTS =0.0_gp
real(gp) :: ePV =0.0_gp !< pressure term
real(gp) :: energy =0.0_gp !< the functional which is minimized
real(gp) :: e_prev =0.0_gp !< the previous value, to show the delta
real(gp) :: trH_prev=0.0_gp !< the previous value, to show the delta
integer(kind = 8) :: c_obj = 0 !< Storage of the C wrapper object.
end type energy_terms
This construction scheme forces to explicitly impose the save
attribute to the structure when using such object in a module.
Therefore, when this structure is a subobject of another derived type
object, like
!> Used to store results of a DFT calculation.
type, public :: DFT_global_output
real(gp) :: energy, fnoise, pressure !< Total energy, noise over forces and pressure
type(energy_terms) :: energs !< All energy terms
integer :: fdim !< Dimension of allocated forces (second dimension)
real(gp), dimension(:,:), pointer :: fxyz !< Atomic forces
real(gp), dimension(6) :: strten !< Stress Tensor
end type DFT_global_output
one has to impose save
attribute when using this object in a module:
Error: Module variable 'outs' at (1) with a component initialization must have the SAVE attribute
For this reason, it is better to always use explicit constructors in order to make things explicit.
Note the specific names of the above mentioned subprograms. We have used an attribute (null) for the function subprogram and an action (nullify) for the subroutine. Such a convention might help in clarify what is done by the subroutine. Note also that these subroutines have to have the intent(out) specified, such as to highlight that no components comes out undefined from the creators.
A derived type often contains ultimate components which are associated to dynamical memory storage, i.e. allocatable and pointer components. So far we have restricted in BigDFT to pointer components, for backward compatibility with older compilers and for the possibility of explicitly distinguish between shallow copy and deep copy. After constructing a type some methods have to be defined to allocate the memory space associated to it. Therefore the module should also contain the allocators and deallocators of the derived type. In most of the cases these are subroutines, and therefore should be named by (de)allocate_. Here follows an example:
integer :: nvctr_c,nvctr_f,nseg_c,nseg_f
integer, dimension(:,:), pointer :: keyglob
integer, dimension(:,:), pointer :: keygloc
integer, dimension(:), pointer :: keyvloc,keyvglob
end type wavefunctions_descriptors
[...]
!initializations
subroutine allocate_wfd(wfd)
use module_base
implicit none
type(wavefunctions_descriptors), intent(inout) :: wfd
!local variables
integer :: nsegs
nsegs=max(1,wfd%nseg_c+wfd%nseg_f)
wfd%keyvloc=f_malloc_ptr(nsegs,id='wfd%keyvloc')
wfd%keyvglob=f_malloc_ptr(nsegs,id='wfd%keyvglob')
wfd%keyglob=f_malloc_ptr((/2,nsegs/),id='wfd%keyglob')
wfd%keygloc=f_malloc_ptr((/2,nsegs/),id='wfd%keygloc')
END SUBROUTINE allocate_wfd
!> De-Allocate wavefunctions_descriptors
subroutine deallocate_wfd(wfd)
use module_base
implicit none
type(wavefunctions_descriptors) :: wfd
!in case the two objects points to the same target
if (associated(wfd%keyglob, target = wfd%keygloc)) then
!assuming that globals has been created before
call f_free_ptr(wfd%keyglob)
nullify(wfd%keygloc)
else
call f_free_ptr(wfd%keygloc)
call f_free_ptr(wfd%keyglob)
end if
if (associated(wfd%keyvloc, target= wfd%keyvglob)) then
call f_free_ptr(wfd%keyvglob)
nullify(wfd%keyvloc)
else
call f_free_ptr(wfd%keyvloc)
call f_free_ptr(wfd%keyvglob)
end if
END SUBROUTINE deallocate_wfd
Here you can see that the name does not respect the specification, as the routines are called (de)allocate_wfd instead of (de)allocate_wavefunctions_descriptors. This is reasonable when the name of the derived type is often confused with the usual name of the variable associated with it. As wfd appears often in the code as a component of the locreg_descriptors derived type, this makes the concept unambiguous. As often happens, the thumb rule is that one is free to generalize the rule, provided that it is easy to understand the generalization.
To act, the allocators of course need extra information, which is often contained in the structure itself (the number of segments in the example above). Therefore the allocators can only be called when this information is given. In principle, it should be easy to understand for the developers which is the information needed. Also, f_malloc_ptr structure and f_free_ptr routines are used to trace the allocation of the pointer components of intrinsic types. For the derived types pointer components, a good practice is to use the allocate and deallocate statements without stat keyword such as to force crashing is something odd occurs. Also, these subroutines should not have to call f_routine and f_release_routine, as it is more important to trace the calling routine rather then to profile the (de)allocators themselves.
When more complicated operations are needed to initialize a derived type, we refer to corresponding subprograms with _init and _set keywords.